home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / smaltalk / manchest.lha / MANCHESTER / manchester / 2.2 / printOutInLatex.st (.txt) < prev    next >
LaTeX Document  |  1993-07-24  |  22KB  |  573 lines

  1. "    NAME        printOutInLatex
  2.     AUTHOR        iforwyn williams <ifor@cs.man.ac.uk>
  3.     FUNCTION browser prints in LaTeX; you need st80Macros.tex 
  4.     ST-VERSIONS    2.2
  5.     PREREQUISITES     
  6.     CONFLICTS    
  7.     DISTRIBUTION      world
  8.     VERSION        1.1
  9.     DATE    22 Jan 1989
  10. SUMMARY    printOutInLatex
  11.      prints things out in LaTeX. Everything is done in
  12.    terms of macros in /usr/lib/tex/macros/st80Macros.tex (appended).
  13.    (2.2).IWW
  14. 'This is a latex dumper for Smalltalk code.
  15.  It provides a Latex-out menu option in each Browser list.
  16.  Before you file it in, you may like to check that the menus here
  17.  are the same as your present Browser menus, plus the Latex option.
  18.  Search for \LaTeX and check the list against your own browser.
  19.  The latex output expects a file st80Macros.tex, which you should
  20.  have received with this.
  21. % The following contains the LaTeX macros required by the Smalltalk
  22. % pretty printing routine. Every control sequence used by the pretty
  23. % printer is a macro defined in this file
  24. % beware of the duplicated double quotes!
  25. % Minor improvements 9/8/88 alan@uk.ac.man.cs
  26. %##############################################################################
  27. %#                                                                            #
  28. %#                                                                            #
  29. %# This first section contains the macros for the class description headings. #
  30. %#                                                                            #
  31. %#                                                                            #
  32. %##############################################################################
  33. \newcommand{\tabInSource}{}    % so that it may be \renewcommanded
  34. \newcommand{\eolnInSource}{\ }    % so that it may be \renewcommanded
  35. \newcommand{\classSeparator}{\newpage}
  36. \newcommand{\superClass}[1]{{\small\rm superclass}\>{\normalsize\sf #1}\\}
  37. \newcommand{\instanceVariables}[1]{{\small\rm instance variables}
  38.                 \>{\normalsize\sf #1}\\}
  39. \newcommand{\moreInstanceVariables}[1]{\>{\normalsize\sf #1}\\}
  40. \newcommand{\classVariables}[1]{{\small\rm class variables}
  41.                 \>{\normalsize\sf #1}\\}
  42. \newcommand{\moreClassVariables}[1]{\>{\normalsize\sf #1}\\}
  43. \newcommand{\poolDictionaries}[1]{{\small\rm pool dictionaries}
  44.                 \>{\normalsize\sf #1}\\}
  45. \newcommand{\morePoolDictionaries}[1]{\>{\normalsize\sf #1}\\}
  46. \newcommand{\classCategory}[1]{{\small\rm class category}
  47.                 \>{\normalsize\sf #1}}
  48. \newcommand{\composeHeading}[1]{\markright{\timeHeading\ \ \ #1}}
  49. \newcommand{\methodCategory}[1]{\noindent\pagebreak[3]\newline {\Large\rm #1}}
  50. \newcommand{\comment}[1]{ ``{\em #1}\/''}
  51. \newcommand{\commentStart}{\bgroup\protect\renewcommand{\tabInSource}{\rule{2em}{0pt}}\em``}
  52. \newcommand{\commentBreak}{\\[0.5ex]}    % break in long comment
  53. \newcommand{\commentEnd}{\leavevmode\/''\egroup\newline}
  54. \pagestyle{myheadings}\markright{}
  55. \newcommand{\timeHeading}{}
  56. \newcommand{\timeTitle}[1]{\renewcommand{\timeHeading}{#1}\composeHeading{}%
  57. }    % Displays time and version. 
  58. \newenvironment{classHeading}{\pagebreak[3]\begin{tabbing} 
  59.     instance variables \= \kill}{\end{tabbing}\nopagebreak}
  60. \newcommand{\class}[1]{\composeHeading{#1}%
  61. \rule{\linewidth}{.01in}\\{\small\rm class}\>{\Large\bf #1}\\}
  62. % This next env integrates functions of classHeading env and \class.
  63. \newenvironment{classHead}[1]{\composeHeading{#1}%
  64. \pagebreak[3]\begin{tabbing}
  65.     instance variables \= \kill
  66. \rule{\linewidth}{.01in}\\{\small\rm class}\>{\Large\bf #1}\\
  67. }{\end{tabbing}\nopagebreak}
  68. \newenvironment{method}[1]{\pagebreak[2]\begin{list}{}{\setlength{\leftmargin}{0.2in}}\protect\renewcommand{\tabInSource}{\ \ \ }\protect\renewcommand{\eolnInSource}{\nopagebreak[2]\newline\mbox{}}\item {\bf #1 \nopagebreak[3]\newline}\sf}{\protect\renewcommand{\tabInSource}{}\protect\renewcommand{\eolnInSource}{\newline\pagebreak}\end{list}}
  69. %##############################################################################
  70. %#                                                                            #
  71. %#                                                                            #
  72. %# This second section contains the macros for characters used in Smalltalk.  #
  73. %#                                                                            #
  74. %#                                                                            #
  75. %##############################################################################
  76. \newcommand{\plusSymbol}{$+$}        %    +
  77. \newcommand{\minusSymbol}{$-$}        %    -
  78. \newcommand{\multiplySymbol}{$*$}    %    *
  79. \newcommand{\forwardSlash}{$/$}        %    /
  80. \newcommand{\reverseSlash}{$\backslash$}    %    \
  81. \newcommand{\verticalBar}{$\mid$}    %    |
  82. \newcommand{\openSquareBracket}{$[$}    %    [
  83. \newcommand{\closeSquareBracket}{$]$}    %    ]
  84. \newcommand{\openCurlyBracket}{$\{$}    %    {
  85. \newcommand{\closeCurlyBracket}{$\}$}    %    }
  86. \newcommand{\openBracket}{$($}        %    (
  87. \newcommand{\closeBracket}{$)$}        %    )
  88. \newcommand{\ampersand}{\&}        %    &
  89. \newcommand{\hashSymbol}{\#}        %    #
  90. \newcommand{\questionMark}{?}        %    ?
  91. \newcommand{\dollarSymbol}{\$}        %    $
  92. \newcommand{\plingSymbol}{!!}        %    !!
  93. \newcommand{\atSymbol}{@}        %    @
  94. \newcommand{\lessThan}{$<$ }        %    <
  95. \newcommand{\greaterThan}{$>$ }        %    >
  96. \newcommand{\equalsSymbol}{$=$}        %    =
  97. \newcommand{\singleQuote}{'}        %    '
  98. \newcommand{\doubleLeftQuote}{{\tt ""}}    %    ''
  99. \newcommand{\leftArrow}{$\leftarrow$ }    %    <-
  100. \newcommand{\upArrow}{$\uparrow$}    %    ^
  101. \newcommand{\tilderSymbol}{$\sim$}    %    ~
  102. \newcommand{\none}{{\em none}}        % 'none'
  103. 'From Smalltalk-80, version 2, of April 1, 1983 on 30 October 1986 at 8:12:24 pm'!
  104. TimeZone initializeDefaultTimeZone: 0!
  105. Cursor addClassVarName: 'TexCursor'!
  106. !ChangeSet class methodsFor: 'fileIn/Out'!
  107. superclassOrder: classes 
  108.     "Arrange the classes in the collection, classes, in superclass order so the classes can be properly filed in.  Class A must come before class B if A is a superclass of B, or if B is A's metaclass."
  109.     "SystemOrganization superclassOrder: 'System-Changes' "
  110.     ( classes select:
  111.             [:c| ((classes includes: c superclass)
  112.                 or: [(c isKindOf: Metaclass)
  113.                     and: [classes includes: c soleInstance]]
  114.                 ) not ]
  115.     ) inject: OrderedCollection new
  116.       into:
  117.         [:list :top | list addAll: (self superclassOrder: classes under: top). list]
  118. "Fixed so as to enforce alpha ordering as far as possible ---alan"!
  119. superclassOrder: classes under: top
  120.     | subs sift o | 
  121.     "Answer the descendant classes of top which appear in classes"
  122.     subs _ SortedCollection sortBlock: [:x :y| x name <= y name].
  123.     subs addAll: top subclasses.
  124.     sift _ (OrderedCollection with: top class).
  125.     sift addAll: subs.
  126.     o _ OrderedCollection with: top.
  127.     o addAll:
  128.         (sift inject: OrderedCollection new
  129.               into: [:list :sub |
  130.                       (classes includes: sub)
  131.                     ifTrue: [list addAll: (self     superclassOrder: classes
  132.                                                 under: sub)].
  133.                     list]).
  134.     ^o! !
  135. !Cursor class methodsFor: 'class initialization'!
  136. texCursorInitialize
  137.     "initialize the print out in LaTeX cursor - Cursor tex"
  138.     TexCursor _ (Cursor
  139.     extent: 16@16
  140.     fromArray: #(
  141.         2r0
  142.         2r0
  143.         2r0
  144.         2r111110000110011
  145.         2r101010000010010
  146.         2r1000000011110
  147.         2r1011111001100
  148.         2r1001000001100
  149.         2r1001000011110
  150.         2r1001111010010
  151.         2r11101000110011
  152.         2r1000000000
  153.         2r11111000000
  154.         2r0
  155.         2r0
  156.         2r0)
  157.     offset: 0@0)! !
  158. !Cursor class methodsFor: 'constants'!
  159.     "Answer the instance of me that spells TeX."
  160.     ^TexCursor!
  161. ! Cursor texCursorInitialize! 
  162. !Character class methodsFor: 'accessing untypeable characters'!
  163.     "Answer the Character representing a line feed."
  164.     ^self value: 10! !
  165. !WriteStream methodsFor: 'character writing'!
  166.     "Append a linefeed character to the receiver."
  167.     self nextPut: Character lf! !
  168. !Browser methodsFor: 'category list'!
  169. categoryMenu
  170.     "Browser flushMenus"
  171.     category == nil ifTrue:
  172.         [^ ActionMenu labels: 'add category\update\edit all\find class' withCRs
  173.                     lines: #(1 3)
  174.                     selectors: #(addCategory updateCategories editCategories findClass)].
  175.     CategoryMenu == nil ifTrue:
  176.         [CategoryMenu _ ActionMenu
  177.             labels: 'file out\LaTeX out\spawn\add category\rename\remove\update\edit all\find class' withCRs
  178.             lines: #(3 6 8)
  179.             selectors: #(fileOutCategory printOutCategory spawnCategory addCategory renameCategory removeCategory updateCategories editCategories findClass)].
  180.     ^ CategoryMenu! !
  181. !Browser methodsFor: 'class list'!
  182. classMenu
  183.     "Browser flushMenus"
  184.     className == nil ifTrue: [^nil].
  185.     ClassMenu == nil ifTrue:
  186.         [ClassMenu _ ActionMenu
  187.             labels: 'file out\LaTeX out\spawn\spawn hierarchy
  188. hierarchy\definition\comment\protocols
  189. inst var refs\class var refs\class refs
  190. find method
  191. rename\remove' withCRs
  192.             lines: #(4 8 11 12)
  193.             selectors: #(fileOutClass printOutClass spawnClass spawnHierarchy  
  194. showHierarchy editClass editComment editProtocols
  195. browseFieldReferences browseClassVariables browseClassReferences
  196. findMethodAndSelectAlphabetic
  197.  renameClass removeClass)].
  198.     ^ ClassMenu! !
  199. !Browser methodsFor: 'protocol list'!
  200. protocolMenu
  201.     "Browser flushMenus"
  202.     protocol == nil ifTrue:
  203.         [^ ActionMenu labels: 'add protocol' selectors: #(addProtocol)].
  204.     ProtocolMenu == nil ifTrue:
  205.         [ProtocolMenu _ ActionMenu
  206.             labels: 'file out\LaTeX out\spawn\add protocol\rename\remove' withCRs
  207.             lines: #(3)
  208.             selectors: #(fileOutProtocol printOutProtocol spawnProtocol addProtocol renameProtocol removeProtocol)].
  209.     ^ ProtocolMenu! !
  210. !Browser methodsFor: 'selector list'!
  211. selectorMenu
  212.     "Browser flushMenus"
  213.     selector == nil ifTrue: [^ nil].
  214.     MessageMenu == nil ifTrue:
  215.         [MessageMenu _ ActionMenu
  216.             labels: 'file out\LaTeX out\spawn\senders\implementors\messages\move\remove' withCRs
  217.             lines: #(3 6)
  218.             selectors: #(fileOutMessage printOutMessage spawnMethod browseSenders browseImplementors browseMessages moveMethod removeMethod)].
  219.     ^ MessageMenu!
  220. !Browser flushMenus! 
  221. !Browser methodsFor: 'category functions'!
  222. printOutCategory
  223.     SystemOrganization printOutCategory: category! !
  224. !Browser methodsFor: 'class functions'!
  225. printOutClass
  226.     self selectedClass printOutClass! !
  227. !Browser methodsFor: 'protocol functions'!
  228. printOutProtocol
  229.     self selectedClass printOutProtocol: protocol! !
  230. !Browser methodsFor: 'selector functions'!
  231. printOutMessage
  232.     |fileName |
  233.     self selectedClass printOutMessage: selector! !
  234. ClassDescription addClassVarName: 'CharacterMappingDictionary'!
  235. !ClassDescription methodsFor: 'private'!
  236. initializeLatexCharacterMappingDictionary
  237.     "Initializes the LaTeX character mapping dictionary"
  238.     CharacterMappingDictionary _ Dictionary new.
  239.     CharacterMappingDictionary at: $% put: '\%'.
  240.     CharacterMappingDictionary at: $~ put: '\tilderSymbol '.
  241.     CharacterMappingDictionary at: $@ put: '\atSymbol '.
  242.     CharacterMappingDictionary at: $' put: '\singleQuote '.
  243.     CharacterMappingDictionary at: $" put: '\doubleLeftQuote '.
  244.     CharacterMappingDictionary at: $- put: '\minusSymbol '.
  245.     CharacterMappingDictionary at: $* put: '\multiplySymbol '.
  246.     CharacterMappingDictionary at: $+ put: '\plusSymbol '.
  247.     CharacterMappingDictionary at: $^ put: '\upArrow '.
  248.     CharacterMappingDictionary at: $\ put: '\reverseSlash '.
  249.     CharacterMappingDictionary at: $/ put: '\forwardSlash '.
  250.     CharacterMappingDictionary at: $$ put: '\dollarSymbol  '.
  251.     CharacterMappingDictionary at: $!! put: '\plingSymbol  '.
  252.     CharacterMappingDictionary at: $| put: '\verticalBar  '.
  253.     CharacterMappingDictionary at: $_ put: '\leftArrow '.
  254.     CharacterMappingDictionary at: $& put: '\ampersand '.
  255.     CharacterMappingDictionary at: $[ put: '\openSquareBracket '.
  256.     CharacterMappingDictionary at: $] put: '\closeSquareBracket '.
  257.     CharacterMappingDictionary at: ${ put: '\openCurlyBracket '.
  258.     CharacterMappingDictionary at: $} put: '\closeCurlyBracket '.
  259.     CharacterMappingDictionary at: $( put: '\openBracket '.
  260.     CharacterMappingDictionary at: $) put: '\closeBracket '.
  261.     CharacterMappingDictionary at: $< put: '\lessThan '.
  262.     CharacterMappingDictionary at: $> put: '\greaterThan '.
  263.     CharacterMappingDictionary at: $= put: '\equalsSymbol '.
  264.     CharacterMappingDictionary at: $# put: '\hashSymbol '.
  265.     CharacterMappingDictionary at: $? put: '\questionMark '.
  266.     CharacterMappingDictionary at: Character cr put: '\eolnInSource '.
  267.     CharacterMappingDictionary at: Character tab put: '\tabInSource '.
  268.     CharacterMappingDictionary at: Character space put: '\  '! !
  269. !ClassDescription methodsFor: 'fileIn/Out'!
  270. printCategoryChunk: aString on: aFileStream 
  271.     "print category definition on aFileStream"
  272.     aFileStream cr; cr; nextPut: $!!.
  273.     aFileStream nextChunkPut:
  274.                 self name , ' methodsFor: ' , '''' , aString , ''''! !
  275. !ClassDescription methodsFor: 'printOutInLatex'!
  276. printClassOn: fileStream
  277.     "Create a readable version of the message category aString, and  
  278.     send to a printer."
  279.     Cursor tex
  280.         showWhile: 
  281.             self printOutStartUp: fileStream.
  282.             self printOutTimeStamp: fileStream with: self name asString.
  283.             self printOutOn: fileStream.
  284.             self printOutCloseDown: fileStream.
  285.             fileStream shorten; close]!
  286. printOutClass
  287.     "Create a readable version of the class definition."
  288.     | fileName fileStream |
  289.     Cursor tex
  290.         showWhile: 
  291.             [fileName _ FillInTheBlank request: 'LaTeX file'
  292.                 initialAnswer: (FileDirectory fixFileName: self name , '.tex').
  293.             fileName = '' ifFalse: [
  294.             self printClassOn: (FileStream fileNamed: fileName)]]!
  295. printMethodChunk: aSelector on: aFileStream moveSource: moveSource toFile: fileIndex 
  296.     "Print the source code for the method associated with the argument  
  297.     selector onto  
  298.     the fileStream. aFileStream, and, for backup, if the argument  
  299.     moveSource (a Boolean)  
  300.     is true, also set the file index within the method to be the argument  
  301.     fileIndex."
  302.     | position |
  303.     aFileStream lf.
  304.     Cursor write showWhile: [moveSource
  305.             ifTrue: 
  306.                 [position _ aFileStream position.
  307.                 aFileStream nextChunkPut: (self sourceCodeAt: aSelector).
  308.                 (self compiledMethodAt: aSelector)
  309.                     setSourcePosition: position inFile: fileIndex]
  310.             ifFalse: [aFileStream lf; nextChunkPut: (self sourceCodeAt: aSelector)]]!
  311. printOutProtocol: aString 
  312.     "Create a readable version of the protocol (message category) aString, and  
  313.     send to a printer."
  314.     | fileName fileStream |
  315.     Cursor tex
  316.         showWhile: 
  317.             [fileName _ FillInTheBlank request: 'LaTeX file'
  318.                 initialAnswer: (FileDirectory fixFileName: (self name, '-', aString , '.tex')).
  319.             fileName = '' ifFalse: [
  320.             fileStream _ FileStream fileNamed: fileName.
  321.             self printOutStartUp: fileStream.
  322.             self printOutTimeStamp: fileStream with: self name, ' $>$ ', aString..
  323.             self printOutDefinitionOn: fileStream.
  324.             self printOutProtocol: aString on: fileStream.
  325.             self printOutCloseDown: fileStream.
  326.             fileStream shorten; close]]! 
  327. printOutProtocol: aString on: aFileStream 
  328.     "File a description of the receiver's category, aString, onto 
  329.     aFileStream. "
  330.     self
  331.         printOutMacro: '\methodCategory'
  332.         with: aString
  333.         on: aFileStream.
  334.     (self organization listAtCategoryNamed: aString)
  335.         do: [:sel | self printOutMessage: sel on: aFileStream]!
  336. printOutCloseDown: fileStream 
  337.     fileStream nextPutAll: '\end{document} '; lf!
  338. printOutCommentOn: fileStream 
  339.     | comm prev numberOfCharactersOnThisLine |
  340.     comm _ self comment.
  341.     comm size = 0 ifTrue: [^self].
  342.     self
  343.         printOutMacro: '\commentStart'
  344.         with: nil
  345.         on: fileStream.
  346.     prev _ Character space.
  347.     numberOfCharactersOnThisLine _ 0.
  348.     comm do: 
  349.         [:this | 
  350.         numberOfCharactersOnThisLine _ numberOfCharactersOnThisLine + 1.
  351.         (numberOfCharactersOnThisLine > 70 and: [this asInteger <= Character space asInteger])
  352.             ifTrue: 
  353.                 [fileStream lf.
  354.                 numberOfCharactersOnThisLine _ 0].
  355.         ((this = Character tab) | (this = Character cr) and: [prev = Character cr])
  356.             ifTrue: [self
  357.                     printOutMacro: '\commentBreak'
  358.                     with: nil
  359.                     on: fileStream].
  360.         (CharacterMappingDictionary includesKey: this)
  361.             ifTrue: 
  362.                 [fileStream nextPutAll: (CharacterMappingDictionary at: this).
  363.                 this = Character cr
  364.                     ifTrue: 
  365.                         [fileStream lf.
  366.                         numberOfCharactersOnThisLine _ 0]]
  367.             ifFalse: [fileStream nextPut: this].
  368.         prev _ this].
  369.     fileStream lf.
  370.     self
  371.         printOutMacro: '\commentEnd'
  372.         with: nil
  373.         on: fileStream! 
  374. printOutDefinitionOn: fileStream 
  375.     | names first sc |
  376.     self
  377.         printOutMacro: '\begin{classHeading}\class'
  378.         with: self name
  379.         on: fileStream.
  380.     "    printOutMacro: '\begin{classHead}{', self name, '}'
  381.         with: ''
  382.         on: fileStream. "
  383.     sc _ self superclass.
  384.     sc isNil
  385.         ifTrue: [self
  386.                 printOutMacro: '\superClass'
  387.                 with: 'nil'
  388.                 on: fileStream]
  389.         ifFalse: [self
  390.                 printOutMacro: '\superClass'
  391.                 with: sc name
  392.                 on: fileStream].
  393.     names _ self instVarNames.
  394.     names size = 0 ifTrue: [self
  395.             printOutMacro: '\instanceVariables'
  396.             with: '\none'
  397.             on: fileStream].
  398.     names size > 0 ifTrue: [self
  399.             printOutMacro: '\instanceVariables'
  400.             with: (names at: 1)
  401.             on: fileStream].
  402.     names size > 1 ifTrue: [2 to: names size do: [:index | self
  403.                 printOutMacro: '\moreInstanceVariables'
  404.                 with: (names at: index)
  405.                 on: fileStream]].
  406.     names _ self classPool keys asSortedCollection.
  407.     names size = 0
  408.         ifTrue: [self
  409.                 printOutMacro: '\classVariables'
  410.                 with: '\none'
  411.                 on: fileStream]
  412.         ifFalse: 
  413.             [first _ true.
  414.             names do: [:each | first
  415.                     ifTrue: 
  416.                         [self
  417.                             printOutMacro: '\classVariables'
  418.                             with: each
  419.                             on: fileStream.
  420.                         first _ false]
  421.                     ifFalse: [self
  422.                             printOutMacro: '\moreClassVariables'
  423.                             with: each
  424.                             on: fileStream]]].
  425.     names _ self sharedPools.
  426.     names size = 0
  427.         ifTrue: [self
  428.                 printOutMacro: '\poolDictionaries'
  429.                 with: '\none'
  430.                 on: fileStream]
  431.         ifFalse: 
  432.             [first _ true.
  433.             names do: [:each | first
  434.                     ifTrue: 
  435.                         [self
  436.                             printOutMacro: '\poolDictionaries'
  437.                             with: (Smalltalk keyAtValue: each)
  438.                             on: fileStream.
  439.                         first _ false]
  440.                     ifFalse: [self
  441.                             printOutMacro: '\morePoolDictionaries'
  442.                             with: (Smalltalk keyAtValue: each)
  443.                             on: fileStream]]].
  444.     self category ~= nil ifTrue: [self
  445.             printOutMacro: '\classCategory'
  446.             with: self category
  447.             on: fileStream].
  448.     self    printOutMacro: '\end'
  449.             with: 'classHeading'
  450.             on: fileStream
  451.     "self printOutMacro: '\end'
  452.             with: 'classHead'
  453.             on: fileStream"!
  454. printOutMacro: macroName with: argString on: aFileStream 
  455.     aFileStream nextPutAll: macroName.
  456.     argString ~= nil ifTrue: [aFileStream nextPut: ${ ; nextPutAll: argString asString; nextPut: $} ].
  457.     aFileStream lf!
  458. printOutMessage: aString 
  459.     "Create a readable version of the message with selector aString, and  
  460.     send to a printer.
  461.     Defaults to fileOut."
  462.     | fileName |
  463.     Cursor tex
  464.         showWhile: 
  465.             fileName _ FillInTheBlank request: 'LaTeX out on' 
  466.                     initialAnswer: (FileDirectory fixFileName: 
  467.                         self name, '-', aString, '.tex'). 
  468.             fileName = '' ifFalse: [
  469.             self printOutMessage: aString fileName: fileName]]! 
  470. printOutMessage: aString fileName: fileName 
  471.     | fileStream |
  472.     fileStream _ FileStream fileNamed: fileName.
  473.     self printOutStartUp: fileStream.
  474.     self printOutTimeStamp: fileStream with: self name, ' $>>$ ', aString..
  475.     self printOutDefinitionOn: fileStream.
  476.     self
  477.         printOutMacro: '\methodCategory'
  478.         with: 'in ', (self whichCategoryIncludesSelector: aString)
  479.         on: fileStream.
  480.     self printOutMessage: aString on: fileStream.
  481.     self printOutCloseDown: fileStream.
  482.     fileStream close!
  483. printOutMessage: aString on: aFileStream 
  484.     "Create LaTeX file for the method aString"
  485.     | sourceCode bodyStart characterMappingDictionary numberOfCharactersOnThisLine |
  486.     sourceCode _ self sourceCodeAt: aString asSymbol.
  487.     bodyStart _ sourceCode findString: '\' withCRs startingAt: 1.
  488.     bodyStart = 0 ifTrue: ["one liner?" 
  489.                 bodyStart _ (sourceCode findString: '^' startingAt: 1)-1].
  490.     bodyStart > 0
  491.         ifTrue: [self
  492.                 printOutMacro: '\begin{method}'
  493.                 with: (sourceCode copyFrom: 1 to: bodyStart - 1)
  494.                 on: aFileStream]
  495.         ifFalse: 
  496.             [aFileStream nextPutAll: '\begin{method}'; lf; tab; nextPutAll: '\upArrow self'; lf; nextPutAll: '\end{method}'; lf.
  497.             ^self].
  498.     numberOfCharactersOnThisLine _ 0.
  499.     (sourceCode copyFrom: bodyStart + 1 to: sourceCode size)
  500.         do: 
  501.             [:char | 
  502.             numberOfCharactersOnThisLine _ numberOfCharactersOnThisLine + 1.
  503.             (numberOfCharactersOnThisLine > 80 and: [char asInteger <= Character space asInteger])
  504.                 ifTrue: 
  505.                     [aFileStream lf.
  506.                     numberOfCharactersOnThisLine _ 0].
  507.             (CharacterMappingDictionary includesKey: char)
  508.                 ifTrue: 
  509.                     [aFileStream nextPutAll: (CharacterMappingDictionary at: char).
  510.                     char = Character cr
  511.                         ifTrue: 
  512.                             [aFileStream lf.
  513.                             numberOfCharactersOnThisLine _ 0]]
  514.                 ifFalse: [aFileStream nextPut: char]].
  515.     (sourceCode at: sourceCode size)
  516.         ~= Character cr ifTrue: [aFileStream lf].
  517.     aFileStream nextPutAll: '\end{method}'; lf! 
  518. printOutOn: aFileStream 
  519.     "print me out on aFileStream"
  520.     self printOutDefinitionOn: aFileStream.
  521.     self printOutCommentOn: aFileStream.
  522.     self organization categories do: [:heading | self printOutProtocol: heading on: aFileStream].!
  523. printOutStartUp: fileStream 
  524.     fileStream nextPutAll: '\documentstyle{article}';lf.
  525.     fileStream nextPutAll: '\input{a4l}';lf.
  526.     fileStream nextPutAll: '\input st80Macros ';lf.
  527.     fileStream nextPutAll: '\begin{document}';lf.
  528.     self initializeLatexCharacterMappingDictionary!
  529. printOutTimeStamp: aStream with: aString
  530.     | dateTime |
  531.     dateTime _ Time dateAndTimeNow.
  532.     aStream nextPutAll:
  533.             '\timeTitle{',
  534.             (dateTime at: 1) printString,
  535.             ' at ', (dateTime at: 2) printString, 
  536.             '\ \ \ \bf ', aString, '}'
  537.         ; lf! !
  538. !SystemOrganizer methodsFor: 'fileIn/Out'!
  539. printOutCategory: category 
  540.     | aFileStream |
  541.     Cursor tex
  542.         showWhile: 
  543.             [Transcript refresh; cr; cr; show: 'Printing out category: ' , category.
  544.             aFileStream _ FileStream fileNamed: (category , '.tex').
  545.             Object printOutStartUp: aFileStream.
  546.             Object printOutTimeStamp: aFileStream with: category.
  547.             self printOutCategory: category on: aFileStream.
  548.             Object printOutCloseDown: aFileStream.
  549.             aFileStream shorten; close]! 
  550. printOutCategory: category on: aFileStream 
  551.     | class first |
  552.     first _ true.
  553.     (self superclassOrder: category)
  554.         do: 
  555.             [:class | 
  556.             first
  557.                 ifTrue: [first _ false]
  558.                 ifFalse: [class
  559.                         printOutMacro: '\classSeparator'
  560.                         with: nil
  561.                         on: aFileStream].
  562.             class printOutOn: aFileStream.
  563.             class class printOutOn: aFileStream]! !
  564. !FileDirectory class methodsFor: 'utilities'!
  565. fixFileName: aFileName
  566.     "Make the file name a valid file name."
  567.     ^((aFileName copyReplaceAll: ' ' with: '_')
  568.         copyReplaceAll: '*' with: '%')
  569.         copyReplaceAll: ':' with: '='! !
  570. ' sent:
  571.     r6 goodies 2/2/88
  572.     Headings, order of printout, bugs in comments, etc improved 15/7/88.
  573.